home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Celestin Apprentice 5
/
Apprentice-Release5.iso
/
Environments
/
PowerMacOberon feb96
/
Source
/
Files.Mod
(
.txt
)
< prev
next >
Wrap
Oberon Text
|
1995-10-17
|
25KB
|
633 lines
Syntax10.Scn.Fnt
Syntax10i.Scn.Fnt
StampElems
Alloc
17 Oct 95
Syntax10b.Scn.Fnt
FoldElems
MarkElems
Alloc
MODULE Files; (* CM/HM/CS
IMPORT SYSTEM, Sys, Kernel, Dsp, Directories, Strings;
CONST
nofbufs = 4; (* buffers per file *)
bufSize = 4096; (* size of each buffer *)
fileTabSize = 64; (* maximum number of simultaneously open access paths *)
none = -1;
noErr = 0; (* no error *)
fnfErr = -43; (* file not found error *)
File* = POINTER TO FileDesc;
Buffer = POINTER TO BufDesc;
FileDesc = RECORD
name: Sys.Str63; (*name under which the file is to be registered (pure file name)*)
spec: Sys.FSSpec; (*file specification for MacOS*)
refNum: INTEGER; (*file reference number*)
registered: BOOLEAN; (*TRUE if opened with Old or if Registered*)
ix: INTEGER; (*file table index*)
swapper: INTEGER; (*index of next buffer to swap *)
len, time, date: LONGINT;
buf: ARRAY nofbufs OF Buffer
END;
BufDesc = RECORD
f: File;
changed: BOOLEAN;
org, size: LONGINT;
data: ARRAY bufSize OF SYSTEM.BYTE
END;
Rider* = RECORD
res*: LONGINT;
eof*: BOOLEAN;
buf: Buffer;
org, offset: LONGINT
END;
B2 = ARRAY 2 OF CHAR;
B4 = ARRAY 4 OF CHAR;
B8 = ARRAY 8 OF CHAR;
(*----- LoaderOld has to be the first variable in the data segment *)
LoaderOld: PROCEDURE (spec: Sys.FSSpec; VAR res: INTEGER);
LoaderGetPaths: PROCEDURE; (*unused*)
tempno: LONGINT;
nofpaths: INTEGER;
fileTab: ARRAY fileTabSize OF LONGINT; (* = File *)
PROCEDURE^ DeleteFile (spec: Sys.FSSpec; VAR res: INTEGER);
PROCEDURE
SetStr255 (VAR in: ARRAY OF CHAR; VAR out: Sys.Str255);
VAR i: INTEGER;
BEGIN
i := 0; WHILE in[i] # 0X DO out[i+1] := in[i]; INC(i) END;
out[0] := CHR(i)
END SetStr255;
PROCEDURE
MakeSpec (VAR name: ARRAY OF CHAR; VAR spec: Sys.FSSpec; VAR res: INTEGER);
VAR s: Sys.Str255; startupDir: Directories.Directory; n: ARRAY 256 OF CHAR;
BEGIN
COPY (name, n);
IF n[0] = "$" THEN
startupDir := Directories.Startup ();
Strings.Delete(n, 0, 1); Strings.Insert(Directories.delimiter, 0, n); Strings.Insert(startupDir.path, 0, n)
END;
SetStr255(n, s);
res := Sys.FSMakeFSSpec(0, 0, s, spec)
(*name with path: vRefNum and parID are ignored; name without path: 0, 0 means default directory*)
END MakeSpec;
PROCEDURE
GetName (spec: Sys.FSSpec; VAR path, name: ARRAY OF CHAR);
VAR s: Sys.Str255; v, res, i, j: INTEGER; d: LONGINT; sp: Sys.FSSpec; buf: ARRAY 128 OF CHAR;
BEGIN
j := 128; s := ""; v := spec.vRefNum; d := spec.parID;
REPEAT
DEC(j); buf[j] := ":";
res := Sys.FSMakeFSSpec(v, d, s, sp);
FOR i := ORD(sp.name[0]) TO 1 BY -1 DO DEC(j); buf[j] := sp.name[i] END;
d := sp.parID
UNTIL d = 1;
i := 0; REPEAT path[i] := buf[j]; INC(i); INC(j) UNTIL j = 127;
path[i] := 0X;
FOR i := 0 TO ORD(spec.name[0])-1 DO name[i] := spec.name[i+1] END;
name[i] := 0X
END GetName;
PROCEDURE
GetTempName (VAR name: Sys.Str63);
VAR n, i: LONGINT;
BEGIN
INC(tempno); n := tempno; name := " Oberon.Tmp.0000000000"; name[0] := CHR(21); i := 21;
WHILE n # 0 DO
name[i] := CHR(n MOD 10 + ORD("0")); n := n DIV 10; DEC(i)
END GetTempName;
PROCEDURE
GetIndex (VAR ix: INTEGER);
BEGIN
FOR ix := 0 TO fileTabSize -1 DO
IF fileTab[ix] = 0 THEN RETURN END
END;
HALT(21) (*too many files open*)
END GetIndex;
PROCEDURE
GetFileDate (spec: Sys.FSSpec; VAR t, d: LONGINT; VAR res: INTEGER);
VAR pb: Sys.CInfoPBFileRec;
BEGIN
pb.ioCompletion := 0; pb.ioNamePtr := SYSTEM.ADR(spec.name);
pb.ioVRefNum := spec.vRefNum; pb.ioDirID := spec.parID; pb.ioFDirIndex := 0;
Sys.PBHGetFInfo(SYSTEM.VAL(Sys.CInfoPBFilePtr, SYSTEM.ADR(pb)));
res := pb.ioResult; ASSERT(res = noErr);
Sys.ConvertTime(pb.ioFlMdDat, t, d)
END GetFileDate;
PROCEDURE
OpenFile (f: File; permssn: SHORTINT);
VAR res: INTEGER;
BEGIN (*f exists on disk*)
res := Sys.FSpOpenDF(f.spec, permssn, f.refNum);
ASSERT((res = noErr) OR (res = -49), 22); (* workaround: accept error -49 *)
IF nofpaths = fileTabSize - 1 THEN
Kernel.GC;
IF nofpaths = fileTabSize - 1 THEN res := Sys.FSClose(f.refNum); HALT(21) END
END;
INC(nofpaths);
GetIndex(f.ix); fileTab[f.ix] := SYSTEM.VAL(LONGINT, f);
GetFileDate(f.spec, f.time, f.date, res); ASSERT(res = noErr, 23)
END OpenFile;
PROCEDURE
ThisFile (spec: Sys.FSSpec): File;
VAR i, j, len: INTEGER; f: File;
BEGIN
len := ORD(spec.name[0]);
FOR i := 0 TO fileTabSize - 1 DO
IF fileTab[i] # 0 THEN
f := SYSTEM.VAL(File, fileTab[i]);
IF (f.spec.vRefNum = spec.vRefNum) & (f.spec.parID = spec.parID) & (ORD(f.spec.name[0]) = len) THEN
j := 1;
WHILE (j <= len) & (CAP(spec.name[j]) = CAP(f.spec.name[j])) DO INC(j) END;
IF j > len THEN Dsp.String("--- found"); Dsp.Ln; RETURN f END
END
END
END;
RETURN NIL
END ThisFile;
PROCEDURE
RenameFile (spec: Sys.FSSpec; VAR newName: Sys.Str63; VAR res: INTEGER);
(*newName is pure file name => renames only in same directory*)
VAR newSpec: Sys.FSSpec; s: Sys.Str255; i: INTEGER;
BEGIN
FOR i := 0 TO ORD(newName[0]) DO s[i] := newName[i] END;
res := Sys.FSMakeFSSpec(spec.vRefNum, spec.parID, s, newSpec);
IF res = noErr THEN DeleteFile(newSpec, res) END;
res := Sys.FSpRename(spec, s);
END RenameFile;
PROCEDURE
DeleteFile (spec: Sys.FSSpec; VAR res: INTEGER);
(*if specified file is in fileTab then unregister it else delete it*)
VAR f: File; temp: Sys.Str63;
BEGIN
f := ThisFile(spec);
IF f = NIL THEN res := Sys.FSpDelete(spec)
ELSE (*make it a temporary*)
GetTempName(temp); RenameFile(f.spec, temp, res);
IF res = noErr THEN f.registered := FALSE; f.spec.name := temp; f.name := temp END
END DeleteFile;
PROCEDURE
Create (f: File);
(*called for temporary files if one of their buffers gets read or written*)
VAR res: INTEGER;
BEGIN (*f.ix = none*)
GetTempName(f.spec.name); (*rest of f.spec already ok*)
DeleteFile(f.spec, res);
res := Sys.FSpCreate(f.spec, Sys.ApplSig, Sys.FileSig, Sys.smSystemScript); ASSERT(res = noErr);
OpenFile(f, Sys.fsRdWrPerm)
END Create;
PROCEDURE
ReadBlock (refNum, posmode: INTEGER; pos, count: LONGINT; VAR buf: ARRAY OF SYSTEM.BYTE; VAR res: INTEGER);
BEGIN
res := Sys.SetFPos(refNum, posmode, pos);
IF res = noErr THEN res := Sys.FSRead(refNum, count, SYSTEM.ADR(buf)) END
END ReadBlock;
PROCEDURE
WriteBlock (refNum: INTEGER; pos, count: LONGINT; VAR buf: ARRAY OF SYSTEM.BYTE; VAR res: INTEGER);
VAR logEOF: LONGINT; allocSize: LONGINT;
BEGIN
res := Sys.GetEOF(refNum, logEOF); ASSERT(res = noErr);
IF (pos + count) > logEOF THEN
allocSize := pos + count - logEOF;
res := Sys.Allocate(refNum, allocSize); ASSERT(res = noErr);
res := Sys.SetEOF(refNum, pos + count); ASSERT(res = noErr)
END;
res := Sys.SetFPos(refNum, Sys.fsFromStart, pos); ASSERT(res = noErr);
res := Sys.FSWrite(refNum, count, SYSTEM.ADR(buf))
END WriteBlock;
PROCEDURE
Flush (buf: Buffer);
VAR f: File; res: INTEGER;
BEGIN
IF buf.changed THEN
f := buf.f;
IF f.ix = none THEN Create(f) END;
WriteBlock(f.refNum, buf.org, buf.size, buf.data, res);
buf.changed := FALSE
END Flush;
PROCEDURE
Old* (name: ARRAY OF CHAR): File;
VAR spec: Sys.FSSpec; res: INTEGER; f: File; i: INTEGER;
BEGIN
IF name = "" THEN RETURN NIL END;
(*IF name = "DUMP" THEN Dump; RETURN NIL END;*)
MakeSpec(name, spec, res);
IF res # noErr THEN
i := 0; WHILE (name[i] # 0X) & (name[i] # ":") DO INC(i) END;
IF name[i] = 0X THEN LoaderOld(spec, res) END
END;
IF res = noErr THEN (*found in current dir, paths or appl.dir*)
f := ThisFile(spec);
IF f = NIL THEN
NEW(f); f.spec := spec; f.name := f.spec.name;
OpenFile(f, Sys.fsRdWrPerm);
res := Sys.GetEOF(f.refNum, f.len); ASSERT(res = noErr);
f.registered := TRUE; f.swapper := -1
END
ELSE f := NIL
END;
RETURN f
END Old;
PROCEDURE
New* (name: ARRAY OF CHAR): File;
VAR f: File; res: INTEGER;
BEGIN
NEW(f); MakeSpec(name, f.spec, res); f.name := f.spec.name;
f.ix := none; f.len := 0; f.refNum := -1; f.time := 0; f.date := 0; f.swapper := -1; f.registered := FALSE;
RETURN f
END New;
PROCEDURE
Close* (f: File);
VAR i: INTEGER;
BEGIN
IF f.ix = none THEN Create(f) END;
i := 0;
WHILE (i < nofbufs) & (f.buf[i] # NIL) DO Flush(f.buf[i]); INC(i) END
END Close;
PROCEDURE
Register* (f: File);
(* no registration if f.registered, i.e. opened with Old or already Registered before*)
VAR res: INTEGER; path, name: ARRAY 128 OF CHAR;
BEGIN
IF f.ix = none THEN (*opened with New but not yet created; f.spec already specifies f.name*)
DeleteFile(f.spec, res);
res := Sys.FSpCreate(f.spec, Sys.ApplSig, Sys.FileSig, Sys.smSystemScript); ASSERT(res = noErr);
OpenFile(f, Sys.fsRdWrPerm)
ELSIF ~f.registered THEN
RenameFile(f.spec, f.name, res);
IF res = noErr THEN f.spec.name := f.name END
END;
f.registered := TRUE;
Close(f);
GetName(f.spec, path, name); Directories.notify(Directories.insert, path, name)
END Register;
PROCEDURE
Delete* (name: ARRAY OF CHAR; VAR res: INTEGER);
(** return codes: res = 0: file deleted; res = 3: name is not well formed *)
VAR spec: Sys.FSSpec; path, nm: ARRAY 128 OF CHAR;
BEGIN
MakeSpec(name, spec, res);
IF (res # noErr) & (res # fnfErr) THEN res := 3; RETURN END;
GetName(spec, path, nm);
IF res = noErr THEN DeleteFile(spec, res) END;
IF res = noErr THEN res := 0; Directories.notify(Directories.delete, path, nm) ELSE res := 2 END
END Delete;
PROCEDURE
Rename* (old, new: ARRAY OF CHAR; VAR res: INTEGER);
(** return codes: res = 0: file renamed; res = 1: new name already exists and is now associated with the new file;
res = 2: old name is not in directory; res = 3: name is not well formed; res = 5: other error *)
VAR oldSpec, newSpec, spec: Sys.FSSpec; f: File; retval, i, j: INTEGER;
oldPath, newPath, oldName, newName: ARRAY 128 OF CHAR;
BEGIN
res := 0;
MakeSpec(old, oldSpec, retval); IF retval # noErr THEN res := 2; RETURN END;
MakeSpec(new, newSpec, retval); IF ~ ((retval = noErr) OR (retval = fnfErr)) THEN res := 3; RETURN END;
GetName(oldSpec, oldPath, oldName); GetName(newSpec, newPath, newName);
IF retval # fnfErr THEN
DeleteFile(newSpec, retval);
IF retval = noErr THEN res := 1 END
END;
IF (oldSpec.vRefNum = newSpec.vRefNum) & (oldSpec.parID = newSpec.parID) THEN (*same directory*)
RenameFile(oldSpec, newSpec.name, retval); ASSERT(retval = 0);
f := ThisFile(oldSpec);
IF f # NIL THEN f.spec.name := newSpec.name; f.name := newSpec.name END
ELSE (*move to other directory*)
MakeSpec(newPath, spec, retval); ASSERT(retval = 0);
retval := Sys.FSpCatMove(oldSpec, spec);
IF retval = noErr THEN
IF f # NIL THEN
MakeSpec(new, newSpec, retval); f.spec.parID := newSpec.parID
END
END;
IF retval # noErr THEN res := 5 END
END;
IF res <= 1 THEN
Directories.notify(Directories.delete, oldPath, oldName);
Directories.notify(Directories.insert, newPath, newName)
END Rename;
PROCEDURE
Purge* (f: File);
VAR i, res: INTEGER;
BEGIN
FOR i := 0 TO nofbufs-1 DO
IF f.buf[i] # NIL THEN f.buf[i].org := -1; f.buf[i] := NIL END
END;
IF f.ix # none THEN
res := Sys.SetEOF(f.refNum, 0);
GetFileDate(f.spec, f.time, f.date, res)
END;
f.len := 0; f.swapper := -1
END Purge;
PROCEDURE
GetDate* (f: File; VAR time, date: LONGINT);
BEGIN
time := f.time; date := f.date
END GetDate;
PROCEDURE
Base* (VAR r: Rider): File;
BEGIN
RETURN r.buf.f
END Base;
PROCEDURE
Pos* (VAR r: Rider): LONGINT;
BEGIN
RETURN r.org + r.offset
END Pos;
PROCEDURE
Length* (f: File): LONGINT;
BEGIN
RETURN f.len
END Length;
PROCEDURE
Set* (VAR r: Rider; f: File; pos: LONGINT);
VAR org, offset, i: LONGINT; buf: Buffer; res: INTEGER;
BEGIN
IF pos > f.len THEN pos := f.len ELSIF pos < 0 THEN pos := 0 END;
offset := pos MOD bufSize; org := pos - offset;
i := 0;
WHILE (i < nofbufs) & (f.buf[i] # NIL) & (org # f.buf[i].org) DO INC(i) END;
IF i < nofbufs THEN
IF f.buf[i] = NIL THEN (*f.buf[i..bufSize-1] empty*)
NEW(buf); buf.changed := FALSE; buf.org := -1; buf.f := f; f.buf[i] := buf
ELSE (*org = f.buf[i].org*)
buf := f.buf[i]
END
ELSE (*all buffers full => swap*)
f.swapper := (f.swapper + 1) MOD nofbufs;
buf := f.buf[f.swapper]; Flush(buf)
END;
IF buf.org # org THEN
IF org = f.len THEN buf.size := 0
ELSE
IF f.ix = none THEN Create(f) END;
IF f.len - org < bufSize THEN buf.size := f.len - org ELSE buf.size := bufSize END;
ReadBlock(f.refNum, Sys.fsFromStart, org, buf.size, buf.data, res)
END;
buf.org := org; buf.changed := FALSE
END;
r.buf := buf; r.org := org; r.offset := offset; r.eof := FALSE; r.res := 0
END Set;
(* Data in files is stored in little endian format: the least significant byte gets the least address in the file. Thus the read data must
be converted to big endian (as the PowerPC is a big endian machine) by exchanging the most significant byte with the least
significant byte. Furthermore the ordering of the bits in a set has changed: On the 68k and x86 the bit 0 is the rightmost bit, on the
PowerPC the bit 0 is the leftmost bit. So the bits have to be exchanged too. *)
PROCEDURE
Read* (VAR r: Rider; VAR x: SYSTEM.BYTE);
VAR buf: Buffer; offset: LONGINT;
BEGIN
buf := r.buf; offset := r.offset;
IF r.org # buf.org THEN
Set(r, buf.f, r.org + offset); buf := r.buf; offset := r.offset
END;
IF offset < buf.size THEN
x := buf.data[offset]; r.offset := offset + 1; RETURN
ELSIF r.org + offset < buf.f.len THEN
Set(r, r.buf.f, r.org + offset);
x := r.buf.data[0]; r.offset := 1
ELSE
x := 0X; r.eof := TRUE
END Read;
PROCEDURE
ReadBytes* (VAR r: Rider; VAR x: ARRAY OF SYSTEM.BYTE; n: LONGINT);
VAR xpos, min, restInBuf, offset: LONGINT; buf: Buffer;
BEGIN
ASSERT(n <= LEN(x));
xpos := 0; buf := r.buf; offset := r.offset;
WHILE n > 0 DO
IF (r.org # buf.org) OR (offset >= bufSize) THEN
Set(r, buf.f, r.org + offset);
buf := r.buf; offset := r.offset
END;
restInBuf := buf.size - offset;
IF restInBuf = 0 THEN r.res := n; r.eof := TRUE; RETURN
ELSIF n > restInBuf THEN min := restInBuf
ELSE min := n
END;
SYSTEM.MOVE(SYSTEM.ADR(buf.data[offset]), SYSTEM.ADR(x[xpos]), min);
INC(offset, min);
r.offset := offset;
INC(xpos, min); DEC(n, min)
END;
r.res := n; r.eof := FALSE
END ReadBytes;
PROCEDURE
ReadInt* (VAR R: Rider; VAR x: INTEGER);
VAR b: B2;
BEGIN
Read(R, b[1]); Read(R, b[0]); x := SYSTEM.VAL(INTEGER, b)
END ReadInt;
PROCEDURE
ReadLInt* (VAR R: Rider; VAR x: LONGINT);
VAR b, c: B4;
BEGIN
ReadBytes(R, b, 4);
c[0] := b[3]; c[1] := b[2]; c[2] := b[1]; c[3] := b[0]; x:=SYSTEM.VAL(LONGINT, c)
END ReadLInt;
PROCEDURE
ReadSet* (VAR R: Rider; VAR x: SET);
VAR b, c: B4; y: SET; i: INTEGER;
BEGIN
ReadBytes(R, b, 4);
c[0] := b[3]; c[1] := b[2]; c[2] := b[1]; c[3] := b[0]; y:=SYSTEM.VAL(SET, c);
x := {}; i := 0;
WHILE i < 32 DO
IF i IN y THEN INCL(x, 31 - i) END;
INC(i)
END ReadSet;
PROCEDURE
ReadBool* (VAR R: Rider; VAR x: BOOLEAN);
VAR ch: CHAR;
BEGIN
Read(R, ch); x:= ch # 0X
END ReadBool;
PROCEDURE
ReadReal* (VAR R: Rider; VAR x: REAL);
VAR b, c: B4;
BEGIN
ReadBytes(R, b, 4);
c[0] := b[3]; c[1] := b[2]; c[2] := b[1]; c[3] := b[0]; x:=SYSTEM.VAL(REAL, c)
END ReadReal;
PROCEDURE
ReadLReal* (VAR R: Rider; VAR x: LONGREAL);
VAR b, c: B8;
BEGIN
ReadBytes(R, b, 8);
c[0] := b[7]; c[1] := b[6]; c[2] := b[5]; c[3] := b[4]; c[4] := b[3]; c[5] := b[2]; c[6] := b[1]; c[7] := b[0];
x:=SYSTEM.VAL(LONGREAL, c)
END ReadLReal;
PROCEDURE
ReadString* (VAR R: Rider; VAR x: ARRAY OF CHAR);
VAR i, len: INTEGER; ch: CHAR;
BEGIN
i:=0; len:=SHORT(LEN(x));
REPEAT
Read(R, ch); x[i]:=ch; INC(i)
UNTIL (ch = 0X) OR (i = len);
IF i = len THEN x[len - 1] := 0X END
END ReadString;
PROCEDURE
ReadNum* (VAR R: Rider; VAR x: LONGINT);
VAR s: SHORTINT; ch: CHAR; y: LONGINT;
BEGIN
s := 0; y := 0;
Read(R, ch);
WHILE ch >= 80X DO
INC(y, ASH(LONG(ch) - 128, s)); INC(s, 7);
Read(R, ch)
END;
x := ASH(SYSTEM.LSH(LONG(ch), 25), s - 25) + y
END ReadNum;
PROCEDURE
Write* (VAR r: Rider; x: SYSTEM.BYTE);
VAR buf: Buffer; offset: LONGINT;
BEGIN
buf := r.buf; offset := r.offset;
IF (r.org # buf.org) OR (offset >= bufSize) THEN
Set(r, buf.f, r.org + offset);
buf := r.buf; offset := r.offset
END;
buf.data[offset] := x; buf.changed := TRUE;
IF offset = buf.size THEN INC(buf.size); INC(buf.f.len) END;
r.offset := offset + 1
END Write;
PROCEDURE
WriteBytes* (VAR r: Rider; VAR x: ARRAY OF SYSTEM.BYTE; n: LONGINT);
VAR xpos, min, restInBuf, offset: LONGINT; buf: Buffer;
BEGIN
ASSERT(n <= LEN(x));
xpos := 0; buf := r.buf; offset := r.offset;
WHILE n > 0 DO
IF (r.org # buf.org) OR (offset >= bufSize) THEN
Set(r, buf.f, r.org + offset);
buf := r.buf; offset := r.offset
END;
restInBuf := bufSize - offset;
IF n < restInBuf THEN min := n ELSE min := restInBuf END;
SYSTEM.MOVE(SYSTEM.ADR(x[xpos]), SYSTEM.ADR(buf.data[offset]), min);
INC(offset, min); r.offset := offset;
IF offset > buf.size THEN
INC(buf.f.len, offset - buf.size);
buf.size := offset
END;
INC(xpos, min); DEC(n, min);
buf.changed:=TRUE
END WriteBytes;
PROCEDURE
WriteInt* (VAR R: Rider; x: INTEGER);
VAR b, c: B2;
BEGIN
c := SYSTEM.VAL(B2, x); b[0] := c[1]; b[1] := c[0]; WriteBytes(R, b, 2)
END WriteInt;
PROCEDURE
WriteLInt* (VAR R: Rider; x: LONGINT);
VAR b, c: B4;
BEGIN
c := SYSTEM.VAL(B4, x); b[0] := c[3]; b[1] := c[2]; b[2] := c[1]; b[3] := c[0]; WriteBytes(R, b, 4)
END WriteLInt;
PROCEDURE
WriteSet* (VAR R: Rider; x: SET);
VAR y: SET; i: INTEGER; b, c: B4;
BEGIN
y := {}; i := 0;
WHILE i < 32 DO
IF i IN x THEN INCL(y, 31-i) END;
INC(i)
END;
c := SYSTEM.VAL(B4, y); b[0] := c[3]; b[1] := c[2]; b[2] := c[1]; b[3] := c[0];
WriteBytes(R, b, 4)
END WriteSet;
PROCEDURE
WriteBool* (VAR R: Rider; x: BOOLEAN);
BEGIN
IF x THEN Write(R, 1X) ELSE Write(R, 0X) END
END WriteBool;
PROCEDURE
WriteReal* (VAR R: Rider; x: REAL);
VAR b, c: B4;
BEGIN
c := SYSTEM.VAL(B4, x); b[0] := c[3]; b[1] := c[2]; b[2] := c[1]; b[3] := c[0]; WriteBytes(R, b, 4)
END WriteReal;
PROCEDURE
WriteLReal* (VAR R: Rider; x: LONGREAL);
VAR b, c: B8;
BEGIN
c := SYSTEM.VAL(B8, x);
b[0] := c[7]; b[1] := c[6]; b[2] := c[5]; b[3] := c[4]; b[4] := c[3]; b[5] := c[2]; b[6] := c[1]; b[7] :=c [0];
WriteBytes(R, b, 8)
END WriteLReal;
PROCEDURE
WriteString* (VAR R: Rider; x: ARRAY OF CHAR);
VAR i: INTEGER;
BEGIN
i := 0;
WHILE x[i] # 0X DO INC(i) END;
WriteBytes(R, x, i + 1)
END WriteString;
PROCEDURE
WriteNum* (VAR R: Rider; x: LONGINT);
BEGIN
WHILE (x < -64) OR (x > 63) DO
Write(R, CHR(x MOD 128 + 128));
x:=x DIV 128
END;
Write(R, CHR(x MOD 128))
END WriteNum;
PROCEDURE
CollectFiles; (*called between mark and sweep phase of garbage collector*)
VAR i: LONGINT; s: SET; f: File; res: INTEGER;
BEGIN
FOR i := 0 TO fileTabSize - 1 DO
IF fileTab[i] # 0 THEN
f := SYSTEM.VAL(File, fileTab[i]);
SYSTEM.GET(SYSTEM.VAL(LONGINT, f) - 4, s);
IF ~(Kernel.MarkBit IN s) THEN (*not marked in the mark phase*)
fileTab[i]:=0; DEC(nofpaths);
res := Sys.FSClose(f.refNum); ASSERT(res = noErr);
IF ~f.registered THEN res := Sys.FSpDelete(f.spec) END
END
END
END;
END CollectFiles;
PROCEDURE
Dismount; (*called before PowerMac Oberon is quit*)
VAR s: Sys.Str255; res: INTEGER;
BEGIN
CollectFiles;
s[0] := 0X; res := Sys.FlushVol(SYSTEM.ADR(s), 0);
END Dismount;
(*PROCEDURE
DS (spec: Sys.FSSpec);
VAR i: INTEGER;
BEGIN
Dsp.String("vRefNum="); Dsp.Int(spec.vRefNum);
Dsp.String(", parID="); Dsp.Int(spec.parID);
Dsp.String(" ");
FOR i := 1 TO ORD(spec.name[0]) DO Dsp.Char(spec.name[i]) END;
Dsp.Ln
END DS;
PROCEDURE
Dump;
VAR i, j: INTEGER; f: File;
BEGIN
FOR i := 0 TO fileTabSize -1 DO
IF fileTab[i] # 0 THEN
f := SYSTEM.VAL(File, fileTab[i]);
Dsp.Int(i); Dsp.Char(" ");
FOR j := 1 TO ORD(f.name[0]) DO Dsp.Char(f.name[j]) END; Dsp.String(" (");
Dsp.Int(f.spec.vRefNum); Dsp.Char(" ");
Dsp.Int(f.spec.parID); Dsp.Char(" ");
FOR j := 1 TO ORD(f.spec.name[0]) DO Dsp.Char(f.spec.name[j]) END; Dsp.String(") ");
Dsp.Int(f.refNum);
IF f.registered THEN Dsp.String(" registered ") ELSE Dsp.String(" notRegistered ") END;
Dsp.Int(f.len); Dsp.Char(" ");
FOR j := 0 TO nofbufs-1 DO
IF f.buf[j] = NIL THEN Dsp.Char(".") ELSE Dsp.Char("x") END
END;
Dsp.Ln
END
END Dump;
BEGIN
tempno := ABS(Sys.TickCount());
Kernel.gcQ.Add(CollectFiles);
Kernel.quitQ.Add(Dismount);
nofpaths := 0
END Files.